home *** CD-ROM | disk | FTP | other *** search
/ Shareware Grab Bag / Shareware Grab Bag.iso / 001 / pibt40s3.arc / PIBSCRN2.MOD < prev    next >
Text File  |  1987-04-09  |  41KB  |  772 lines

  1. (*----------------------------------------------------------------------*)
  2. (*       Get_Screen_Text_Line --- Extract text from screen image        *)
  3. (*----------------------------------------------------------------------*)
  4.  
  5. PROCEDURE Get_Screen_Text_Line( VAR Text_Line     : AnyStr;
  6.                                     Screen_Line   : INTEGER;
  7.                                     Screen_Column : INTEGER );
  8.  
  9. (*----------------------------------------------------------------------*)
  10. (*                                                                      *)
  11. (*     Procedure:  Get_Screen_Text_Line                                 *)
  12. (*                                                                      *)
  13. (*     Purpose:    Extracts text from current screen image              *)
  14. (*                                                                      *)
  15. (*     Calling Sequence:                                                *)
  16. (*                                                                      *)
  17. (*       Get_Screen_Text_Line( VAR  Text_Line     : AnyStr;             *)
  18. (*                                  Screen_Line   : INTEGER;            *)
  19. (*                                  Screen_Column : INTEGER );          *)
  20. (*                                                                      *)
  21. (*           Text_Line        --- receives text extracted from screen   *)
  22. (*           Screen_Line      --- line on screen to extract             *)
  23. (*           Screen_Column    --- starting column to extract            *)
  24. (*                                                                      *)
  25. (*     Calls:   None                                                    *)
  26. (*                                                                      *)
  27. (*     Remarks:                                                         *)
  28. (*                                                                      *)
  29. (*        Only the text -- not attributes -- from the screen is         *)
  30. (*        returned.                                                     *)
  31. (*                                                                      *)
  32. (*----------------------------------------------------------------------*)
  33.  
  34. VAR
  35.    First_Pos  : INTEGER;
  36.    Len        : INTEGER;
  37.    I          : INTEGER;
  38.    J          : INTEGER;
  39.    Regs       : RegPack;
  40.    SaveX      : INTEGER;
  41.    SaveY      : INTEGER;
  42.    C          : BYTE;
  43.    Attr       : BYTE;
  44.    LBuffer    : ARRAY[1..256] OF CHAR;
  45.  
  46. BEGIN  (* Get_Screen_Text_Line *)
  47.  
  48.    Screen_Line   := Max( Min( Screen_Line   , Max_Screen_Line ) , 1 );
  49.    Screen_Column := Max( Min( Screen_Column , Max_Screen_Col  ) , 1 );
  50.  
  51.    Text_Line[0]  := #0;
  52.  
  53.    IF Write_Screen_Memory THEN
  54.       BEGIN
  55.  
  56.          First_Pos     := ( ( Screen_Line - 1 ) * Max_Screen_Col +
  57.                             Screen_Column ) SHL 1 - 1;
  58.          Len           := Max_Screen_Col - Screen_Column + 1;
  59.          J             := 0;
  60.  
  61.          IF TimeSharingActive THEN
  62.             BEGIN
  63.                TurnOffTimeSharing;
  64.                Get_Screen_Address( Actual_Screen );
  65.             END;
  66.  
  67.          IF Wait_For_Retrace THEN
  68.             MoveFromScreen( Actual_Screen^.Screen_Image[ First_Pos ],
  69.                             LBuffer[1], Len )
  70.          ELSE
  71.             Move( Actual_Screen^.Screen_Image[ First_Pos ], LBuffer[1], Len SHL 1 );
  72.  
  73.          I := 1;
  74.  
  75.          FOR J := 1 TO Len DO
  76.             BEGIN
  77.                Text_Line[J] := LBuffer[I];
  78.                I            := I + 2;
  79.             END;
  80.  
  81.          Text_Line[0] := CHR( Len );
  82.  
  83.          IF TimeSharingActive THEN
  84.             TurnOnTimeSharing;
  85.  
  86.       END
  87.    ELSE
  88.       BEGIN                        (* Use BIOS to extract line *)
  89.                                    (* Save current position    *)
  90.          SaveX := WhereX;
  91.          SaveY := WhereY;
  92.          J     := 0;
  93.                                    (* Loop over columns to extract *)
  94.  
  95.          FOR I := Screen_Column TO Max_Screen_Col DO
  96.             BEGIN
  97.                                    (* Pick up character *)
  98.  
  99.                ReadCXY( C, I, Screen_Line, Attr );
  100.  
  101.                                    (* Insert character in result string *)
  102.  
  103.                J            := SUCC( J );
  104.                Text_Line[J] := CHR ( C );
  105.  
  106.             END;
  107.                                    (* Set length of string extracted *)
  108.          Text_Line[0] := CHR( J );
  109.                                    (* Restore previous position   *)
  110.          GoToXY( SaveX, SaveY );
  111.  
  112.       END;
  113.  
  114. END    (* Get_Screen_Text_Line *);
  115.  
  116. (*----------------------------------------------------------------------*)
  117. (*                Print_Screen --- Print current screen image           *)
  118. (*----------------------------------------------------------------------*)
  119.  
  120. PROCEDURE Print_Screen;
  121.  
  122. (*----------------------------------------------------------------------*)
  123. (*                                                                      *)
  124. (*     Procedure:  Print_Screen                                         *)
  125. (*                                                                      *)
  126. (*     Purpose:    Prints current screen image (memory mapped area)     *)
  127. (*                                                                      *)
  128. (*     Calling Sequence:                                                *)
  129. (*                                                                      *)
  130. (*        Print_Screen;                                                 *)
  131. (*                                                                      *)
  132. (*     Calls:   None                                                    *)
  133. (*                                                                      *)
  134. (*     Remarks:                                                         *)
  135. (*                                                                      *)
  136. (*        Only the text from the screen is printed, not the attributes. *)
  137. (*                                                                      *)
  138. (*----------------------------------------------------------------------*)
  139.  
  140. VAR
  141.    I         : INTEGER;
  142.    Text_Line : AnyStr;
  143.  
  144. BEGIN  (* Print_Screen *)
  145.  
  146.    FOR I := 1 TO Max_Screen_Line DO
  147.       BEGIN
  148.          Get_Screen_Text_Line( Text_Line, I, 1 );
  149.          WRITELN( Lst , Text_Line );
  150.       END;
  151.  
  152. END    (* Print_Screen *);
  153.  
  154. (*----------------------------------------------------------------------*)
  155. (*        Write_Screen --- Write current screen image to file           *)
  156. (*----------------------------------------------------------------------*)
  157.  
  158. PROCEDURE Write_Screen( Fname : AnyStr );
  159.  
  160. (*----------------------------------------------------------------------*)
  161. (*                                                                      *)
  162. (*     Procedure:  Write_Screen                                         *)
  163. (*                                                                      *)
  164. (*     Purpose:    Write current screen image (memory mapped area) to   *)
  165. (*                 a file.                                              *)
  166. (*                                                                      *)
  167. (*     Calling Sequence:                                                *)
  168. (*                                                                      *)
  169. (*        Write_Screen( Fname : AnyStr );                               *)
  170. (*                                                                      *)
  171. (*           Fname --- Name of file to write screen to                  *)
  172. (*                                                                      *)
  173. (*     Calls:   Open_For_Append                                         *)
  174. (*                                                                      *)
  175. (*     Remarks:                                                         *)
  176. (*                                                                      *)
  177. (*        Only the text from the screen is written, not the attributes. *)
  178. (*        If the file already exists, then the new screen is appended   *)
  179. (*        to the end of the file.                                       *)
  180. (*                                                                      *)
  181. (*----------------------------------------------------------------------*)
  182.  
  183. VAR
  184.    I         : INTEGER;
  185.    Text_Line : AnyStr;
  186.    F         : Text_File;
  187.  
  188. BEGIN  (* Write_Screen *)
  189.  
  190.    IF Open_For_Append( F , Fname , I ) THEN
  191.       BEGIN
  192.  
  193.          FOR I := 1 TO Max_Screen_Line DO
  194.             BEGIN
  195.                Get_Screen_Text_Line( Text_Line, I, 1 );
  196.                WRITELN( F , Text_Line );
  197.             END;
  198.  
  199.             (*$I-*)
  200.          CLOSE( F );
  201.             (*$I+*)
  202.  
  203.       END;
  204.  
  205. END    (* Write_Screen *);
  206.  
  207. (*----------------------------------------------------------------------*)
  208. (*  Write_Graphics_Screen --- Write current screen image to file        *)
  209. (*----------------------------------------------------------------------*)
  210.  
  211. PROCEDURE Write_Graphics_Screen( Fname : AnyStr );
  212.  
  213. (*----------------------------------------------------------------------*)
  214. (*                                                                      *)
  215. (*     Procedure:  Write_Graphics_Screen                                *)
  216. (*                                                                      *)
  217. (*     Purpose:    Write current screen image (memory mapped area) to   *)
  218. (*                 a file.                                              *)
  219. (*                                                                      *)
  220. (*     Calling Sequence:                                                *)
  221. (*                                                                      *)
  222. (*        Write_Graphics_Screen( Fname : AnyStr );                      *)
  223. (*                                                                      *)
  224. (*           Fname --- Name of file to write screen to                  *)
  225. (*                                                                      *)
  226. (*     Calls:   None                                                    *)
  227. (*                                                                      *)
  228. (*     Remarks:                                                         *)
  229. (*                                                                      *)
  230. (*        If the file already exists, then the new screen is appended   *)
  231. (*        to the end of the file.                                       *)
  232. (*                                                                      *)
  233. (*----------------------------------------------------------------------*)
  234.  
  235. VAR
  236.    I         : INTEGER;
  237.    F         : FILE;
  238.  
  239. BEGIN  (* Write_Graphics_Screen *)
  240.  
  241.       (*$I-*)
  242.    ASSIGN( F , Fname );
  243.    REWRITE( F , Graphics_Screen_Length );
  244.  
  245.                                    (* Turn off timesharing while writing screen *)
  246.  
  247.    IF ( MultiTasker = DoubleDos ) THEN
  248.       BEGIN
  249.          TurnOffTimeSharing;
  250.          Get_Screen_Address( Graphics_Screen );
  251.       END;
  252.  
  253.    BlockWrite( F, Graphics_Screen^, 1 );
  254.  
  255.    CLOSE( F );
  256.      (*$I+*)
  257.                                    (* Restore timesharing mode *)
  258.  
  259.    IF ( MultiTasker = DoubleDos ) THEN
  260.       TurnOnTimeSharing;
  261.  
  262. END    (* Write_Graphics_Screen *);
  263.  
  264. (*----------------------------------------------------------------------*)
  265. (*      Get_Screen_Size --- Get maximum rows, columns of display        *)
  266. (*----------------------------------------------------------------------*)
  267.  
  268. PROCEDURE Get_Screen_Size( VAR Rows: INTEGER; VAR Columns: INTEGER );
  269.  
  270. (*----------------------------------------------------------------------*)
  271. (*                                                                      *)
  272. (*     Procedure:  Get_Screen_Size                                      *)
  273. (*                                                                      *)
  274. (*     Purpose:    Gets maximum rows, columns in current display        *)
  275. (*                                                                      *)
  276. (*     Calling Sequence:                                                *)
  277. (*                                                                      *)
  278. (*        Get_Screen_Size( VAR Rows: INTEGER; VAR Columns: INTEGER );   *)
  279. (*                                                                      *)
  280. (*           Rows    --- # of rows in current display                   *)
  281. (*           Columns --- # of columns in current display                *)
  282. (*                                                                      *)
  283. (*     Calls:   Bios                                                    *)
  284. (*                                                                      *)
  285. (*----------------------------------------------------------------------*)
  286.  
  287. VAR
  288.    Regs : RegPack;
  289.    I    : INTEGER;
  290.  
  291. BEGIN  (* Get_Screen_Size *)
  292.                                    (* Set defaults *)
  293.    Regs.AH := $0F;
  294.    INTR( $10 , Regs );
  295.  
  296.    Rows    := 25;
  297.    Columns := MAX( Regs.AH , 80 );
  298.  
  299.                                    (* If EGA installed, check for other *)
  300.                                    (* line values.                      *)
  301.    IF EGA_Installed THEN
  302.       BEGIN
  303.                                    (* Get # of rows in current EGA display *)
  304.          Rows := Get_Rows_For_EGA;
  305.  
  306.                                    (* If 25 lines returned, set        *)
  307.                                    (* EGA 25-line mode to avoid cursor *)
  308.                                    (* problems later on, but only if   *)
  309.                                    (* 80 column text mode.             *)
  310.  
  311.          IF ( ( Rows = 25 ) AND ( Columns = 80 ) ) THEN
  312.             BEGIN
  313.                                    (* Load font for 25 line mode *)
  314.                Regs.AX := $1111;
  315.                Regs.BL := 0;
  316.                INTR( $10, Regs );
  317.                                    (* Reset cursor for 25 line mode *)
  318.                Regs.CX := $0607;
  319.                Regs.AH := 01;
  320.                INTR( $10 , Regs );
  321.  
  322.             END;
  323.  
  324.       END;
  325.  
  326. END    (* Get_Screen_Size *);
  327.  
  328. (*----------------------------------------------------------------------*)
  329. (*      Set_Screen_Size --- Get maximum rows, columns of display        *)
  330. (*----------------------------------------------------------------------*)
  331.  
  332. PROCEDURE Set_Screen_Size( Rows: INTEGER; Columns: INTEGER );
  333.  
  334. (*----------------------------------------------------------------------*)
  335. (*                                                                      *)
  336. (*     Procedure:  Set_Screen_Size                                      *)
  337. (*                                                                      *)
  338. (*     Purpose:    Sets maximum rows, columns in Turbo run-time area    *)
  339. (*                                                                      *)
  340. (*     Calling Sequence:                                                *)
  341. (*                                                                      *)
  342. (*        Set_Screen_Size( Rows: INTEGER; Columns: INTEGER );           *)
  343. (*                                                                      *)
  344. (*           Rows    --- # of rows in current display                   *)
  345. (*           Columns --- # of columns in current display                *)
  346. (*                                                                      *)
  347. (*     Calls:   Clone_Code_Segment                                      *)
  348. (*                                                                      *)
  349. (*----------------------------------------------------------------------*)
  350.  
  351.  
  352. BEGIN  (* Set_Screen_Size *)
  353.  
  354.    Mem[CSeg:Turbo_Screen_Length] := Rows;
  355.    Mem[CSeg:Turbo_Screen_Width ] := Columns;
  356.    CloneCodeSegment( Turbo_Screen_Length , 1 );
  357.    CloneCodeSegment( Turbo_Screen_Width  , 1 );
  358.  
  359. END    (* Set_Screen_Size *);
  360.  
  361. (*----------------------------------------------------------------------*)
  362. (*      Set_EGA_Text_Mode --- Set character set, cursor for EGA         *)
  363. (*----------------------------------------------------------------------*)
  364.  
  365. PROCEDURE Set_EGA_Text_Mode( EGA_Rows : INTEGER );
  366.  
  367. (*----------------------------------------------------------------------*)
  368. (*                                                                      *)
  369. (*     Procedure:  Set_EGA_Text_Mode                                    *)
  370. (*                                                                      *)
  371. (*     Purpose:    Set character set, cursor for EGA                    *)
  372. (*                                                                      *)
  373. (*     Calling Sequence:                                                *)
  374. (*                                                                      *)
  375. (*        Set_EGA_Text_Mode( EGA_Rows : INTEGER );                      *)
  376. (*                                                                      *)
  377. (*           Rows    --- # of rows to set in current display            *)
  378. (*                       25, 35, 43, and 50 lines are supported here.   *)
  379. (*                                                                      *)
  380. (*----------------------------------------------------------------------*)
  381.  
  382. (* STRUCTURED *) CONST
  383.    Table_Ofs : INTEGER = 0;
  384.    Table_Seg : INTEGER = 0;
  385.  
  386. BEGIN (* Set_EGA_Text_Mode *)
  387.  
  388.    Table_Ofs := OFS( Sector_Data );
  389.    Table_Seg := SEG( Sector_Data );
  390.  
  391. INLINE(
  392.   $55                    {                PUSH    BP}
  393.   /$1E                   {                PUSH    DS                      ;Save registers}
  394.                          {;}
  395.   /$FC                   {                CLD                             ; All strings forward}
  396.                          {;}
  397.   /$8B/$86/>EGA_ROWS     {                MOV     AX,[BP+>EGA_Rows]       ; Pick up # lines}
  398.   /$3D/$19/$00           {                CMP     AX,25}
  399.   /$74/$0F               {                JE      Line25}
  400.   /$3D/$23/$00           {                CMP     AX,35}
  401.   /$74/$14               {                JE      Line35}
  402.   /$3D/$2B/$00           {                CMP     AX,43}
  403.   /$74/$44               {                JE      Line43}
  404.   /$3D/$32/$00           {                CMP     AX,50}
  405.   /$74/$49               {                JE      Line50}
  406.                          {;                                               ; Assume 25 lines if bogus}
  407.   /$B8/$11/$11           {Line25:         MOV     AX,$1111                ; Load 8 x 14 font}
  408.   /$B3/$00               {                MOV     BL,0}
  409.   /$CD/$10               {                INT     $10}
  410.   /$E9/$6F/$00           {                JMP     Exit}
  411.                          {;}
  412.   /$B8/$30/$11           {Line35:         MOV     AX,$1130                ; Load 8 x 8 font}
  413.   /$B7/$03               {                MOV     BH,3}
  414.   /$CD/$10               {                INT     $10}
  415.   /$06                   {                PUSH    ES}
  416.   /$1F                   {                POP     DS}
  417.   /$89/$EE               {                MOV     SI,BP                   ; DS:SI point to font}
  418.   /$2E/$C4/$3E/>TABLE_OFS{            CS: LES     DI,[>Table_Ofs]}
  419.   /$BB/$00/$01           {                MOV     BX,$0100                ; Number of chars}
  420.   /$29/$C0               {                SUB     AX,AX}
  421.                          {;}
  422.   /$B9/$04/$00           {Loop35:         MOV     CX,4                    ; Bytes per char}
  423.   /$F3/$A5               {                REPZ    MOVSW}
  424.   /$AB                   {                STOSW}
  425.   /$4B                   {                DEC     BX}
  426.   /$75/$F7               {                JNZ     Loop35}
  427.   /$2E/$A1/>TABLE_OFS    {            CS: MOV     AX,[>Table_Ofs]}
  428.   /$89/$C5               {                MOV     BP,AX                   ; Points to font}
  429.   /$BA/$00/$00           {                MOV     DX,0                    ; Starting char}
  430.   /$B9/$00/$01           {                MOV     CX,$0100                ; Number of chars}
  431.   /$BB/$00/$0A           {                MOV     BX,$0A00                ; Bytes/char}
  432.   /$B8/$10/$11           {                MOV     AX,$1110                ; Load user font}
  433.   /$CD/$10               {                INT     $10}
  434.   /$E9/$3A/$00           {                JMP     Exit}
  435.                          {;}
  436.   /$B8/$12/$11           {Line43:         MOV     AX,$1112                ; Load 8 x 8 font}
  437.   /$B3/$00               {                MOV     BL,0}
  438.   /$CD/$10               {                INT     $10}
  439.   /$E9/$30/$00           {                JMP     Exit}
  440.                          {;}
  441.   /$B8/$30/$11           {Line50:         MOV     AX,$1130                ; Load 8 x 8 font}
  442.   /$B7/$03               {                MOV     BH,3}
  443.   /$CD/$10               {                INT     $10}
  444.   /$06                   {                PUSH    ES}
  445.   /$1F                   {                POP     DS}
  446.   /$89/$EE               {                MOV     SI,BP                   ; DS:SI point to font}
  447.   /$2E/$C4/$3E/>TABLE_OFS{            CS: LES     DI,[>Table_Ofs]}
  448.   /$BB/$00/$01           {                MOV     BX,$0100                ; Number of chars}
  449.                          {;}
  450.   /$B9/$07/$00           {Loop50:         MOV     CX,7                    ; Bytes per char}
  451.   /$F3/$A4               {                REPZ    MOVSB}
  452.   /$46                   {                INC     SI}
  453.   /$4B                   {                DEC     BX}
  454.   /$75/$F7               {                JNZ     Loop50}
  455.   /$2E/$A1/>TABLE_OFS    {            CS: MOV     AX,[>Table_Ofs]}
  456.   /$89/$C5               {                MOV     BP,AX                   ; Points to font}
  457.   /$BA/$00/$00           {                MOV     DX,0                    ; Starting char}
  458.   /$B9/$00/$01           {                MOV     CX,$0100                ; Number of chars}
  459.   /$BB/$00/$07           {                MOV     BX,$0700                ; Bytes/char, block load}
  460.   /$B8/$10/$11           {                MOV     AX,$1110                ; Load user font}
  461.   /$CD/$10               {                INT     $10}
  462.                          {;}
  463.   /$1F                   {Exit:           POP     DS}
  464.   /$5D                   {                POP     BP}
  465. );
  466.  
  467.    CursorOn;
  468.  
  469. END   (* Set_EGA_Text_Mode *);
  470.  
  471. (*----------------------------------------------------------------------*)
  472. (*          WriteSXY --- Write text string to specified row/column      *)
  473. (*----------------------------------------------------------------------*)
  474.  
  475. PROCEDURE WriteSXY (* ( S: AnyStr; X: INTEGER; Y: INTEGER; Color: INTEGER ) *);
  476.  
  477. (*----------------------------------------------------------------------*)
  478. (*                                                                      *)
  479. (*     Procedure:  WriteSXY                                             *)
  480. (*                                                                      *)
  481. (*     Purpose:    Writes text string at specified row and column       *)
  482. (*                 position on screen.                                  *)
  483. (*                                                                      *)
  484. (*     Calling Sequence:                                                *)
  485. (*                                                                      *)
  486. (*        WriteSXY( S: AnyStr; X: INTEGER; Y: INTEGER; Color: INTEGER );*)
  487. (*                                                                      *)
  488. (*           S      --- String to be written                            *)
  489. (*           X      --- Column position to write string                 *)
  490. (*           Y      --- Column position to write string                 *)
  491. (*           Color  --- Color in which to write string                  *)
  492. (*                                                                      *)
  493. (*     Calls:   None                                                    *)
  494. (*                                                                      *)
  495. (*----------------------------------------------------------------------*)
  496.  
  497. BEGIN (* WriteSXY *)
  498.                                    (* Freeze screen for DoubleDos *)
  499.  
  500.    IF ( MultiTasker = DoubleDos ) THEN
  501.       BEGIN
  502.          TurnOffTimeSharing;
  503.          Get_Screen_Address( DesqView_Screen );
  504.       END;
  505.  
  506. INLINE(
  507.   $1E                              {         PUSH  DS                            ;Save data segment register}
  508.                                    {;}
  509.                                    {;  Check if we're using BIOS.}
  510.                                    {;}
  511.   /$F6/$06/>WRITE_SCREEN_MEMORY/$01{         TEST  BYTE [>Write_Screen_Memory],1 ;Direct screen write?}
  512.   /$74/$53                         {         JZ    Bios                          ;No -- go use BIOS}
  513.                                    {;}
  514.                                    {;  Set up for direct screen write.}
  515.                                    {;  Get row position and column positions, and offset in screen buffer.}
  516.                                    {;}
  517.   /$C4/$3E/>DESQVIEW_SCREEN        {         LES   DI,[>DesqView_Screen]         ;Get base address of screen}
  518.   /$8B/$4E/<Y                      {         MOV   CX,[BP+<Y]                    ;CX = Row}
  519.   /$49                             {         DEC   CX                            ;Row to 0..Max_Screen_Line-1 range}
  520.   /$A1/>MAX_SCREEN_COL             {         MOV   AX,[>Max_Screen_Col]          ;Physical screen width}
  521.   /$F7/$E1                         {         MUL   CX                            ;Row * Max_Screen_Col}
  522.   /$8B/$5E/<X                      {         MOV   BX,[BP+<X]                    ;BX = Column}
  523.   /$4B                             {         DEC   BX                            ;Col to 0..Max_Screen_Col-1 range}
  524.   /$01/$D8                         {         ADD   AX,BX                         ;AX = (Row * Max_Screen_Col) + Col}
  525.   /$D1/$E0                         {         SHL   AX,1                          ;Account for attribute bytes}
  526.   /$89/$FB                         {         MOV   BX,DI                         ;Get base offset of screen}
  527.   /$01/$C3                         {         ADD   BX,AX                         ;Add computed offset}
  528.   /$89/$DF                         {         MOV   DI,BX                         ;Move result into DI}
  529.   /$8D/$76/<S                      {         LEA   SI,[BP+<S]                    ;DS:SI will point to S[0]}
  530.   /$A0/>WAIT_FOR_RETRACE           {         MOV   AL,[<Wait_For_Retrace]        ;Grab this before changing DS}
  531.   /$8C/$D2                         {         MOV   DX,SS                         ;Move SS...}
  532.   /$8E/$DA                         {         MOV   DS,DX                         ; into DS}
  533.   /$8A/$0C                         {         MOV   CL,[SI]                       ;CL = Length(S)}
  534.   /$E3/$70                         {         JCXZ  Exit                          ;If string empty, Exit}
  535.   /$46                             {         INC   SI                            ;DS:SI points to S[1]}
  536.   /$8A/$66/<COLOR                  {         MOV   AH,[BP+<Color]                ;AH = Attribute}
  537.   /$FC                             {         CLD                                 ;Set direction to forward}
  538.   /$D0/$D8                         {         RCR   AL,1                          ;If we don't wait for retrace, ...}
  539.   /$73/$1A                         {         JNC   Mono                          ; use "Mono" routine}
  540.                                    {;}
  541.                                    {;  Color routine (used only when RetraceMode is True) **}
  542.                                    {;}
  543.   /$BA/>CRT_STATUS                 {         MOV   DX,>CRT_Status                ;Point DX to CGA status port}
  544.   /$AC                             {GetNext: LODSB                               ;Load next character into AL}
  545.                                    {                                             ; AH already has Attr}
  546.   /$89/$C3                         {         MOV   BX,AX                         ;Store video word in BX}
  547.                                    {;}
  548.   /$EC                             {WaitNoH: IN    AL,DX                         ;Get 6845 status}
  549.   /$A8/$01                         {         TEST  AL,1                          ;Wait for horizontal}
  550.   /$75/$FB                         {         JNZ   WaitNoH                       ; retrace to finish}
  551.                                    {;}
  552.   /$FA                             {         CLI                                 ;Turn off interrupts}
  553.   /$EC                             {WaitH:   IN    AL,DX                         ;Get 6845 status again}
  554.   /$A8/$01                         {         TEST  AL,1                          ;Wait for horizontal retrace}
  555.   /$74/$FB                         {         JZ    WaitH                         ; to start}
  556.                                    {;}
  557.   /$89/$D8                         {Store:   MOV   AX,BX                         ;Restore attribute}
  558.   /$AB                             {         STOSW                               ; and then to screen}
  559.   /$FB                             {         STI                                 ;Allow interrupts}
  560.   /$E2/$EC                         {         LOOP  GetNext                       ;Get next character}
  561.   /$E9/$4D/$00                     {         JMP   Exit                          ;Done}
  562.                                    {;}
  563.                                    {;  Mono routine (used whenever Wait_For_Retrace is False) **}
  564.                                    {;}
  565.   /$AC                             {Mono:    LODSB                               ;Load next character into AL}
  566.                                    {                                             ; AH already has Attr}
  567.   /$AB                             {         STOSW                               ;Move video word into place}
  568.   /$E2/$FC                         {         LOOP  Mono                          ;Get next character}
  569.                                    {;}
  570.   /$E9/$46/$00                     {         JMP   Exit                          ;Done}
  571.                                    {;}
  572.                                    {;  Use BIOS to display string (if Write_Screen is False) **}
  573.                                    {;}
  574.   /$8A/$76/<Y                      {Bios:    MOV   DH,[BP+<Y]                    ;Get starting row}
  575.   /$FE/$CE                         {         DEC   DH                            ;Drop by one for BIOS}
  576.   /$8A/$56/<X                      {         MOV   DL,[BP+<X]                    ;Get starting column}
  577.   /$FE/$CA                         {         DEC   DL                            ;Drop for indexing}
  578.   /$FE/$CA                         {         DEC   DL                            ;}
  579.   /$8D/$76/<S                      {         LEA   SI,[BP+<S]                    ;DS:SI will point to S[0]}
  580.   /$8C/$D0                         {         MOV   AX,SS                         ;Move SS...}
  581.   /$8E/$D8                         {         MOV   DS,AX                         ; into DS}
  582.   /$31/$C9                         {         XOR   CX,CX                         ;Clear out CX}
  583.   /$8A/$0C                         {         MOV   CL,[SI]                       ;CL = Length(S)}
  584.   /$E3/$2D                         {         JCXZ  Exit                          ;If string empty, Exit}
  585.   /$46                             {         INC   SI                            ;DS:SI points to S[1]}
  586.   /$52                             {         PUSH  DX                            ;Save X and Y}
  587.   /$1E                             {         PUSH  DS                            ;Save string address}
  588.   /$56                             {         PUSH  SI                            ;}
  589.   /$FC                             {         CLD                                 ;Forward direction}
  590.                                    {;}
  591.   /$B4/$02                         {Bios1:   MOV   AH,2                          ;BIOS Position cursor}
  592.   /$B7/$00                         {         MOV   BH,0                          ;Page zero}
  593.   /$5E                             {         POP   SI                            ;Get S address}
  594.   /$1F                             {         POP   DS                            ;}
  595.   /$5A                             {         POP   DX                            ;X and Y}
  596.   /$FE/$C2                         {         INC   DL                            ;X + 1}
  597.   /$52                             {         PUSH  DX                            ;Save X and Y}
  598.   /$1E                             {         PUSH  DS                            ;Save strin address}
  599.   /$56                             {         PUSH  SI}
  600.   /$51                             {         PUSH  CX                            ;Push length}
  601.   /$CD/$10                         {         INT   $10                           ;Call BIOS to move to (X,Y)}
  602.   /$59                             {         POP   CX                            ;Get back length}
  603.   /$5E                             {         POP   SI                            ;Get String address}
  604.   /$1F                             {         POP   DS                            ;}
  605.   /$AC                             {         LODSB                               ;Next character into AL}
  606.   /$1E                             {         PUSH  DS                            ;Save String address}
  607.   /$56                             {         PUSH  SI                            ;}
  608.   /$51                             {         PUSH  CX                            ;Length left to do}
  609.   /$B4/$09                         {         MOV   AH,9                          ;BIOS Display character}
  610.   /$B7/$00                         {         MOV   BH,0                          ;Display page zero}
  611.   /$8A/$5E/<COLOR                  {         MOV   BL,[BP+<Color]                ;BL = Attribute}
  612.   /$B9/$01/$00                     {         MOV   CX,1                          ;One character}
  613.   /$CD/$10                         {         INT   $10                           ;Call BIOS}
  614.   /$59                             {         POP   CX                            ;Get back length}
  615.   /$E2/$DB                         {         LOOP  Bios1}
  616.                                    {;                                            ;Remove stuff left on stack}
  617.   /$5E                             {         POP   SI}
  618.   /$1F                             {         POP   DS}
  619.   /$5A                             {         POP   DX}
  620.                                    {;}
  621.   /$1F                             {Exit:    POP   DS                            ;Restore DS}
  622. );
  623.                                    (* Unfreeze screen in DoubleDos *)
  624.  
  625.    IF ( MultiTasker = DoubleDos ) THEN
  626.       TurnOnTimeSharing
  627.                                    (* Synchronize screen for TopView *)
  628.  
  629.    ELSE IF ( MultiTasker = TopView ) THEN
  630.       Sync_Screen( ( ( Y - 1 ) * Max_Screen_Col + X ) SHL 1 - 1 , ORD( S[0] ) );
  631.  
  632. END   (* WriteSXY *);
  633.  
  634. (*----------------------------------------------------------------------*)
  635. (*   WriteTTY --- Write character to screen using BIOS write TTY        *)
  636. (*----------------------------------------------------------------------*)
  637.  
  638. PROCEDURE WriteTTY( C: CHAR; Color: INTEGER );
  639.  
  640. (*----------------------------------------------------------------------*)
  641. (*                                                                      *)
  642. (*     Procedure:  WriteTTY                                             *)
  643. (*                                                                      *)
  644. (*     Purpose:    Writes a character to screen using BIOS write TTY    *)
  645. (*                                                                      *)
  646. (*     Calling Sequence:                                                *)
  647. (*                                                                      *)
  648. (*        WriteTTY( C: CHAR; Color: INTEGER );                          *)
  649. (*                                                                      *)
  650. (*           C      --- Character to be written                         *)
  651. (*           Color  --- Color in which to write character               *)
  652. (*                                                                      *)
  653. (*     Calls:   BIOS                                                    *)
  654. (*                                                                      *)
  655. (*----------------------------------------------------------------------*)
  656.  
  657. BEGIN (* WriteTTY *)
  658.  
  659.    INLINE(
  660.             $B4/$09               {   MOV   Ah,9        ;BIOS display character}
  661.            /$8A/$46/$20           {   MOV   Al,C' '     ;Blank}
  662.            /$B7/$00               {   MOV   BH,0        ;}
  663.            /$8A/$5E/$04           {   MOV   BL,[BP+4]   ;Color}
  664.            /$B9/$01/$00           {   MOV   CX,1        ;One character}
  665.            /$CD/$10               {   INT   $10         ;Call BIOS}
  666.            /$B4/$0E               {   MOV   Ah,$0E      ;BIOS display character}
  667.            /$8A/$46/$06           {   MOV   Al,[BP+6]   ;Ch}
  668.            /$B7/$00               {   MOV   BH,0        ;}
  669.            /$CD/$10               {   INT   $10         ;Call BIOS}
  670.          );
  671.  
  672. END   (* WriteTTY *);
  673.  
  674. (*----------------------------------------------------------------------*)
  675. (*       Set_Graphics_Colors --- Set colors for graphics mode           *)
  676. (*----------------------------------------------------------------------*)
  677.  
  678. PROCEDURE Set_Graphics_Colors( EGA_On : BOOLEAN;
  679.                                GMode  : INTEGER;
  680.                                FG     : INTEGER;
  681.                                BG     : INTEGER );
  682.  
  683. (*----------------------------------------------------------------------*)
  684. (*                                                                      *)
  685. (*     Procedure:  Set_Graphics_Colors                                  *)
  686. (*                                                                      *)
  687. (*     Purpose:    Sets colors for graphics modes                       *)
  688. (*                                                                      *)
  689. (*     Calling Sequence:                                                *)
  690. (*                                                                      *)
  691. (*        Set_Graphics_Colors( EGA_On: BOOLEAN; GMode: INTEGER;         *)
  692. (*                             FG    : INTEGER; BG   : INTEGER );       *)
  693. (*                                                                      *)
  694. (*           EGA_On --- TRUE if EGA installed                           *)
  695. (*           GMode  --- Graphics mode to set                            *)
  696. (*           FG     --- Foreground color                                *)
  697. (*           BG     --- Background color                                *)
  698. (*                                                                      *)
  699. (*----------------------------------------------------------------------*)
  700.  
  701. VAR
  702.    Regs: RegPack;
  703.  
  704. BEGIN (* Set_Graphics_Colors *)
  705.  
  706.                                    (* Request 640x200 graphics mode    *)
  707.    IF EGA_On THEN
  708.       BEGIN (* Set up EGA mode *)
  709.  
  710.          WITH Regs DO
  711.             BEGIN
  712.                Regs.Ah := 0;
  713.                Regs.Al := GMode;
  714.                INTR( $10, Regs );
  715.             END;
  716.                                    (* Set graphics border color *)
  717.         WITH Regs DO
  718.            BEGIN
  719.               Regs.Ah := 16;
  720.               Regs.Al := 01;
  721.               Regs.Bh := BG;
  722.               Regs.Bl := 0;
  723.               INTR( $10, Regs );
  724.           END;
  725.                                    (* Set graphics foreground color *)
  726.         WITH Regs DO
  727.            BEGIN
  728.               Regs.Ah := 16;
  729.               Regs.Al := 00;
  730.               Regs.Bh := FG;
  731.               Regs.Bl := 1;
  732.               INTR( $10, Regs );
  733.           END;
  734.                                    (* Set graphics background color *)
  735.         WITH Regs DO
  736.            BEGIN
  737.               Regs.Ah := 16;
  738.               Regs.Al := 00;
  739.               Regs.Bh := BG;
  740.               Regs.Bl := 0;
  741.               INTR( $10, Regs );
  742.            END;
  743.                                    (* Set foreground intensity *)
  744.  
  745.         IF ( FG > 7 ) THEN
  746.            WITH Regs DO
  747.               BEGIN
  748.                  Regs.Ah := 16;
  749.                  Regs.Al := 03;
  750.                  Regs.Bh := FG;
  751.                  Regs.Bl := 0;
  752.                  INTR( $10, Regs );
  753.               END;
  754.  
  755.       END   (* Set up EGA mode *)
  756.    ELSE
  757.       BEGIN (* Set up CGA mode *)
  758.  
  759.          WITH Regs DO
  760.             BEGIN
  761.                Regs.Ah := 0;
  762.                Regs.Al := GMode;
  763.                INTR( $10, Regs );
  764.             END;
  765.  
  766.          GraphBackGround( FG );
  767.  
  768.       END   (* Set up CGA mode *);
  769.  
  770. END   (* Set_Graphics_Colors *);
  771.  
  772.